home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Comp / excess.pl < prev    next >
Text File  |  1989-04-14  |  3KB  |  107 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
  5.  
  6. % Fix code containing illegal (excess) temporary variables,
  7. % those temporaries numbered X9 or higher.
  8.  
  9. % Excess phase contains three passes:
  10. %    1.  Backwards pass to reallocate permanents and excess temporaries
  11. %         as permanents.  As in permalloc, variables whose last use
  12. %        is later in the program get lower numbered locations.
  13. %    2.  Forward pass to fix up all get and put instructions whose
  14. %        second operand is now a permanent.
  15. %    3.  Forward pass to change the 'unsafe_value' annotation to a
  16. %        'value' annotation for all temporaries.  This finishes the
  17. %        work started by valvar.
  18.  
  19. excess(Objcode,Objcode4) :-
  20.    excess(Objcode,Objcode2,_,_),
  21.    cleanup(Objcode2,Objcode3),
  22.    temp_value(Objcode3,Objcode4).
  23.  
  24. % Pass 1.
  25.  
  26. excess([I|Rest],[NI|NR],NewPerm,NewMap) :-
  27.    excess(Rest,NR,NextPerm,Map),
  28.    fix_excess(I,NI,NextPerm,NewPerm,Map,NewMap).
  29.  
  30. excess([],[],1,[]).
  31.  
  32. fix_excess(get(Ann,A,B),get(Ann,NA,NB),NextPerm,NewPerm,Map,NewMap) :-
  33.    fix_temp(A,NA,NextPerm,NextPerm2,Map,NextMap),
  34.    fix_temp(B,NB,NextPerm2,NewPerm,NextMap,NewMap).
  35.  
  36. fix_excess(put(Ann,A,B),put(Ann,NA,NB),NextPerm,NewPerm,Map,NewMap) :-
  37.    fix_temp(A,NA,NextPerm,NextPerm2,Map,NextMap),
  38.    fix_temp(B,NB,NextPerm2,NewPerm,NextMap,NewMap).
  39.  
  40. fix_excess(unify(Ann,A),unify(Ann,NA),NextPerm,NewPerm,Map,NewMap) :-
  41.    fix_temp(A,NA,NextPerm,NewPerm,Map,NewMap).
  42.  
  43. fix_excess(I,I,NextPerm,NextPerm,Map,Map).
  44.  
  45. % allocate a new permanent in place of old permanent or excess temporary.
  46.  
  47. fix_temp(A,NA,NextPerm,NewPerm,Map,NewMap) :-
  48.    nonvar(A), A=x(I), nonvar(I), I>8, !, 
  49.    add_perm(A,NA,NextPerm,NewPerm,Map,NewMap).
  50.  
  51. fix_temp(A,NA,NextPerm,NewPerm,Map,NewMap) :-
  52.    nonvar(A), A=y(_), !, 
  53.    add_perm(A,NA,NextPerm,NewPerm,Map,NewMap).
  54.  
  55. fix_temp(A,A,NextPerm,NextPerm,Map,Map).
  56.  
  57.     add_perm(A,NA,NextPerm,NewPerm,Map,NewMap) :-
  58.         inmap(A,Map,NA), !,
  59.         NewMap = Map, NewPerm = NextPerm.
  60.     add_perm(A,NA,NextPerm,NewPerm,Map,NewMap) :-
  61.         NA = y(NextPerm),
  62.         NewPerm is NextPerm+1,
  63.         NewMap = [pair(A,NA)|Map].
  64.  
  65. % check whether variable has been reallocated yet, and if so, what it has been
  66. % reallocated to.
  67.  
  68. inmap(A,[pair(A,NA)|_],NA) :- !.
  69. inmap(A,[_|Rest],NA) :- inmap(A,Rest,NA), !.
  70.  
  71. % Pass 2.
  72.  
  73. cleanup([put(Ann,A,B),get(structure,S,C)|Rest],
  74.     [put(Ann,A,x(8)),get(structure,S,x(8))|NRest]) :-
  75.    nonvar(A), nonvar(B), nonvar(C), A = y(_), A = B, B = C, !,
  76.    cleanup(Rest,NRest).
  77.  
  78. cleanup([put(Ann,A,B)|Rest],
  79.     [put(value,B,x(8)),put(structure,A,x(8))|NRest]) :-
  80.    nonvar(Ann), Ann = structure, nonvar(B), B = y(_), !, 
  81.    cleanup(Rest,NRest).
  82.  
  83. cleanup([put(Ann,A,B)|Rest],
  84.     [put(Ann,A,x(8)),get(variable,B,x(8))|NRest]) :-
  85.    nonvar(B), B = y(_), !, 
  86.    cleanup(Rest,NRest).
  87.  
  88. cleanup([get(Ann,A,B)|Rest],
  89.     [put(value,B,x(8)),get(Ann,A,x(8))|NRest]) :-
  90.    nonvar(B), B = y(_), !, 
  91.    cleanup(Rest,NRest).
  92.  
  93. cleanup([I|Rest],[I|NRest]) :- cleanup(Rest,NRest).
  94.  
  95. cleanup([],[]).
  96.  
  97. % Pass 3.
  98.  
  99. temp_value([I|Rest], [NI|NRest]) :-
  100.     I=..[N,unsafe_value,X|RI],
  101.     nonvar(X), X=x(_), !,
  102.     NI=..[N,value,X|RI],
  103.     temp_value(Rest, NRest).
  104. temp_value([I|Rest], [I|NRest]) :-
  105.     temp_value(Rest, NRest).
  106. temp_value([], []).
  107.